DepthToDiv Function

public function DepthToDiv(column, depth) result(d)

Return which division corresponds to given depth

Arguments

Type IntentOptional Attributes Name
type(SoilColumn), intent(in) :: column
real(kind=float), intent(in) :: depth

Return Value integer


Variables

Type Visibility Attributes Name Initial
real, public :: depth_computed
logical, public :: founddiv

Source Code

 FUNCTION DepthToDiv &
!
 (column, depth) &
!
 RESULT (d)

IMPLICIT NONE

!Arguments with intent in
TYPE(SoilColumn), INTENT(IN)  :: column
REAL (KIND = float), INTENT(IN) :: depth

!local declarations:
INTEGER :: d
LOGICAL :: founddiv
REAL :: depth_computed

!-------------------------end of declarations----------------------------------
founddiv = .FALSE.
depth_computed = 0.
DO d = 1, column % divs
  depth_computed = depth_computed + column % div (d) % thickness
  IF (depth_computed == depth) THEN
    founddiv = .TRUE.
    RETURN
  END IF
END DO

IF (.NOT. founddiv) THEN
  CALL Catch ('error', 'SoilProperties', &
       'division not found corresponding to depth: ' , &
        argument = ToString(depth))
     
  
END IF

END FUNCTION DepthToDiv